perm filename LINED.PAL[AL,HE] blob sn#602794 filedate 1981-07-22 generic text, type C, neo UTF8
COMMENT āŠ—   VALID 00013 PAGES
C REC  PAGE   DESCRIPTION
C00001 00001
C00002 00002	.TITLE	LINE EDITOR
C00004 00003	 Character definitions:
C00006 00004	 Dispatch table for line editor commands:
C00008 00005	 Terminal I/O routines:  INCHR, CRLF, TYPSTR, TYPCHR.
C00011 00006	 INITED:  Initialization routine.
C00013 00007	 MAIN PROGRAM
C00015 00008	 INSTR:  The line editor routine.
C00019 00009		[INCHR:	Easy routines.]
C00027 00010		[INSTR:	LINSRT]
C00030 00011		[INSTR:	LDEL, LKILLR, LKILLL]
C00036 00012		[INSTR:	LGETM, LDEFM]
C00043 00013	 DATA DEFINITIONS
C00045 ENDMK
CāŠ—;
.TITLE	LINE EDITOR

; MACRO definitions & etc.

BUFLEN	== 80.			;LENGTH OF THE INPUT BUFFER.

.MACRO 	PUSH X			; PUSH X ONTO SYSTEM STACK
	MOV	X,-(SP)
	.ENDM

.MACRO	POP X			; POP X FROM SYSTEM STACK
	MOV	(SP)+, X
	.ENDM

.MACRO  CALL X			; JUMP TO SUBROUTINE
	JSR	PC,X
	.ENDM

.MACRO 	TYPMSG	MSG		; TYPE MSG ON SCREEN
	MOV	#MSG,R4		 ;SET UP STARTING ADDRESS
	CALL	TYPSTR		 ;TYPE THE STRING;
	CALL	CRLF   		 ;TYPE A CRLF
	.ENDM

.MACRO 	TYPEIT	MSG		; TYPE MSG ON SCREEN
	PUSH	R4		 ;SAVE R4
	MOV	#MSG,R4		 ;SET UP STARTING ADDRESS
	CALL	TYPSTR		 ;TYPE THE STRING.  NO CRLF!
	POP	R4
	.ENDM

.=1000

.INSRT STUFF.PAL[ARM,RV]

; Character definitions:

NULL	== 00
CTLB	== 02	;Control characters are computed by subtracting octal 100
CTLC	== 03	;from the character representation.
CTLD	== 04
CTLE	== 05
CTLF	== 06
CTLG	== 07
CTLH	== 10
CTLI	== 11
CTLK	== 13
CTLL	== 14
CTLO	== 17
CTLR	== 22
CTLS	== 23
CTLW	== 27
CTLX	== 30
CTLZ	== 32
TAB	== 11	;same as CTLI
LF	== 12	;actually control-J
CR	== 15	;actually control-M
ALT	== 33
BS	== 10
BELL	== 07	;control-G also
SPACE	== 40
RUBOUT	== 177
MINCH	== SPACE  ;First character = space
MAXCH	== 176	  ;Last character = righty curly bracket, }

;Control char definitions:
GETOLD	== CTLO		;Restore last line typed RRR
SKIPR	== CTLS		;Skip right to next char typed
SKIPL	== CTLB		;Skip left  "   "    "     "
; Dispatch table for line editor commands:

DISPTB:	.WORD	LBAD   		;Null     00	No good
	.WORD	LBAD   		;Ctrl-A	  01	No good
	.WORD	LSKIPL		;Ctrl-B   02	Skip left
	.WORD	LCLEAR		;Ctrl-C	  03	Clear line editor
	.WORD	LDEL		;Ctrl-D	  04	Delete char
	.WORD	LTOEND		;Ctrl-E	  05	To end of line
	.WORD	LTOFRO		;Ctrl-F	  06	To front of line
	.WORD	LGETM		;Ctrl-G	  07	Expand a macro definition
	.WORD	LMOVEL		;Ctrl-H	  10	Move one char left
	.WORD	LINSRT		;Ctrl-I	  11	Insert text in front of cursor
	.WORD	LBAD		;Ctrl-J	  12	
	.WORD	LKILLR		;Ctrl-K	  13	Kill Right to char
	.WORD	LKILLL		;Ctrl-L	  14	Kill Left to char
	.WORD	LCR		;Ctrl-M	  15	Carriage return - exit
	.WORD	LINSRT		;Ctrl-N	  16	Insert text
	.WORD	LBAD		;Ctrl-O	  17	
	.WORD	LBAD		;Ctrl-P	  20	
	.WORD	LBAD		;Ctrl-Q	  21	
	.WORD	LREPT		;Ctrl-R	  22	Repeat last SKIP cmd
	.WORD	LSKIPR		;Ctrl-S	  23	Skip right
	.WORD	LXPOSE		;Ctrl-T	  24	Transpose previous 2 chars
	.WORD	LBAD		;Ctrl-U	  25	
	.WORD	LBAD		;Ctrl-V	  26	
	.WORD	LWORD		;Ctrl-W	  27	Skip to next word
	.WORD	LMOVER		;Ctrl-X	  30	Move right one char
	.WORD	LDDT		;Ctrl-Y	  31	Enter DDT (testing purposes)
	.WORD	LDEFM		;Ctrl-Z	  32	Define a macro
; Terminal I/O routines:  INCHR, CRLF, TYPSTR, TYPCHR.

; INCHR reads a single char from the VT05 and puts it in R0.
; It doesn't echo the characters.

INCHR:	TST	LMODE		;Reading from TTY?
	BEQ	10$		;Yes - go read
	TSTB	@LMACPT		;No  - reading macro.  End of macro def?
	BNE	5$		 ;not yet - keep reading from macro def.
	CLR	LMODE		 ;yes - put us in TTY mode
	BR	10$		 ;and go read from TTY
5$:	MOVB	@LMACPT,R0	;Put current macro char in R0 to return
	INC	LMACPT		 ;and increment macro ptr.
	BR	20$
10$:   	TSTB 	KBIS		;Anything typed on VT05?
	BPL 	10$  		; No
	MOVB 	KBIR,R0		; Read the char
	BIC 	#177600,R0	;Clear all but low 7 bits
20$:	RTS 	PC


; CRLF types a CRLF on the terminal.
CRLF:	TYPEIT	CRLFX
	RTS	PC
CRLFX:  .BYTE	15,12,0,0


;"TYPSTR" outputs a string, ending with a zero character.  A pointer to
;the start of the string must be loaded into R4.  

TYPSTR:	PUSH	R0
	BR	2$
1$:	JSR	PC,TYPCHR	;TYPE THIS CHARACTER
2$:	MOVB	(R4)+,R0	;GET A CHARACTER
	BNE	1$		;END OF LINE?
	POP	R0
	RTS 	PC		;Done

;"TYPBUF" outputs a string, ending with a zero character.  A pointer to
;the start of the string must be loaded into R4.  It keeps LINPTR in synch
;with the cursor position.  Note that R4 does not change!

TYPBUF:	PUSH	R0
	MOV	R4,LINPTR	;SET INITIAL VALUE FOR LINE PTR.
	BR	2$
1$:	JSR	PC,TYPCHR	;TYPE THIS CHARACTER
	INC	LINPTR		;BUMP PTR
2$:	MOVB	@LINPTR,R0	;GET A CHARACTER
	BNE	1$		;END OF LINE?
	POP	R0
	RTS 	PC		;Done

TYPCHR:	TSTB 	KBOS		;VT05: Is it available?
	BPL	TYPCHR		;No
	MOVB 	R0,KBOR		;Output a byte to it.
	CMP 	#12,R0		;Was it a line feed?
	BNE 	5$     		;If not that code, then done.
	CLR 	R0		;Otherwise, output 3 nulls.
	JSR 	PC,TYPCHR	;
	JSR 	PC,TYPCHR	;
	BR	TYPCHR		;Direct jump; it will return to caller.
5$:    	RTS 	PC		;Return.
; INITED:  Initialization routine.

INITED:	PUSH	R0
	PUSH	R1
	MOV	LINBEG,LINPTR	;NEXT PLACE TO PUT A CHAR.
	MOV	#BUFLEN,R0	;NOW CLEAR THE BUFFER.
	MOV	LINBEG,R1
5$:	CLRB	(R1)+
	SOB	R0,5$
	MOV	LINBEG,LINEND	;Set up ptr to end of buffer
	DEC	LINEND		; (means no chars are in it yet)
	MOV	#1,LINRPT	;Initialize repeat count to 1
	POP	R1
	POP	R0
	RTS	PC


; BACKUP backs up the cursor until LINPTR = R1.
BACKUP:	PUSH	R2
	PUSH	R0
       	MOV	LINPTR,R2	;Calculate how many spaces to back up 
	SUB	R1,R2		; = CurPos - FinalPos
	TST	R2		;Consistency check - positive backup?
	BLE	10$
5$:	MOV	#BS,R0		;Back up one position
	CALL	TYPCHR
	SOB	R2,5$		; do it this many times
10$:	MOV	R1,LINPTR	;Set up ptr into line buffer at right place.
	POP	R0
	POP	R2
    	RTS	PC


; MOVEUP moves the cursor forwards until LINPTR = R1.
MOVEUP:	PUSH	R2
	PUSH	R0
       	MOV	R1,R2		;Calculate how many chars to move forward
	SUB	LINPTR,R2
	TST	R2		;Consistency check - positive move?
	BLE	10$
5$:	MOVB	@LINPTR,R0	;Type the current char & move right one spot
	CALL	TYPCHR
	INC	LINPTR		;bump ptr to next char in buffer.
	SOB	R2,5$		; do it this many times
10$:	POP	R0
	POP	R2
       	RTS	PC
; MAIN PROGRAM

START:	RESET
        MOV 	#1000,SP	;Set up the stack
       	TYPMSG	BEGMSG   

	CALL	INITED		;INITIALIZATION
	CLRB	LASTCM 		;NO LAST CMD 
	CLRB	LASTSE		;AND NO LAST CHAR SEARCHED FOR.
	MOV	#10.,R0		;CLEAR OUT MACRO DEF ADDR'S
	MOV	#LMACAD,R1
5$:	CLR	(R1)+
	SOB	R0,5$

LOOP:	TYPEIT	MSG1		;ASK FOR A LINE OF INPUT.
	CALL	INSTR		;Read a string, put in LINBUF.
	TYPEIT	MSG2		;SAY WHAT THE INPUT WAS
	TYPEIT	LINBUF
	TYPEIT	MSG3
	CALL	CRLF
	CALL	CRLF		;EMPTY LINE
	BR	LOOP

BEGMSG:	.ASCIZ	/LINE EDITOR TESTING ROUTINE/
MSG1:	.ASCIZ	/TYPE A LINE TO ME: /
MSG2:	.ASCIZ	/LINE INPUT WAS:   "/
MSG3:	.ASCIZ	/"/
.EVEN
; INSTR:  The line editor routine.
; Note that, at all times (except for periods of flux) the pointer LINPTR
; and the position of the cursor in the line are in correspondence.

INSTR:	CALL	INCHR		;Read a char, put in R0.
	CMPB	R0,#GETOLD	;Retrieve old line buffer?  Only one chance!
	BEQ	LRETYP		;Yes - go do it
	CALL	INITED		;Otherwise initialize the line buffer
	BR	MAINLP		; and go process the char.
LRETYP:	CMP	LINEND,LINBEG 	;Were any chars in buffer?
	BLO	GETCHR		; no - ignore request.
	MOV	LINBEG,R4	;Type out the old buffer.
	CALL   	TYPBUF   	;Type out the old buffer.
	MOV	LINBEG,R1	;Now back up cursor until it's at front of line.
	CALL	BACKUP

GETCHR:	CALL	INCHR		;Get a char, put it in R0.
MAINLP:	MOV	#1,LINRPT	;Assume one repetition unless otherwise specified
CHKCHR:	MOV	LINRPT,R4	;Put repeat count in R4 for routine to use.
       	CMPB	R0,#ALT  	;Is it a control char?
	BLT	10$		; yes - go process it as a command char.
	BEQ	LALT		; ALT - expect a repeat count now. RRR
	CMPB	R0,#RUBOUT	;Also enter routine if it's RUBOUT
	BEQ	LMOVEL
	CMPB	R0,#MINCH	;Is it a valid char?
	BLT	1$		; no - complain
	CMPB	R0,#MAXCH	; yes - add to buffer and echo it.
	BLE	4$
1$:	JMP	LBAD
4$:	CALL	TYPCHR		;A character - Echo the char
	MOVB	R0,@LINPTR		;Store in buffer
	CMP	LINPTR,LINEND		;Was it at the end of the buffer?
	BLOS	5$			;No - don't add to cntr.
	MOV	LINPTR,LINEND		;New end of line
	MOV	LINPTR,R1		;Get ptr to end of buffer.
	CLRB	1(R1)  			;Put null char at end of string to mark it.
5$:	INC	LINPTR			;Points to place to put next char.
	SOB	R4,4$			;Do as many as the repeat count indicates.
	BR	GETCHR			;Go get another char.

10$:	MOV	R0,R1		;Put char in R1 to multiply it
	ASL	R1		;Multiply by two
	JMP 	@DISPTB(R1)	;Enter command routine.

LALT:	CLR	LINRPT		;Now figure out the repeat count.  ALT <n> <cmd>
5$:	CALL	INCHR		;Read a character
	CMPB	R0,#'0		;Is it a digit?
	BLT	20$		 ;No - exit repeat count generation
	CMPB	R0,#'9
	BGT	20$
	SUB	#'0,R0		;Convert character to binary
	MOV	LINRPT,R1	;Put old count in R1
	MUL	#10.,R1		;and multiply by 10
	ADD	R0,R1		;Add new digit
	MOV	R1,LINRPT	;Store new result
	BR	5$		;Go get more digits for repeat count
20$:	TST	LINRPT		;Is repeat count zero?
	BNE 	25$    		;No - continue
	MOV	#1,LINRPT	;Always do it at least once.
25$:	JMP	CHKCHR     	;Enter normal command processing
;	[INCHR:	Easy routines.]

LCR:	CALL	CRLF		;Carriage Return - echo CR+LF
	RTS	PC			;back to caller.

;TAB doesn't work right!  It needs to put spaces in the buffer & add to linend, etc.!
LTAB:	MOV	#TAB,R0		;TAB - just echo the tab
	CALL	TYPCHR
	JMP	GETCHR

LMOVER:	CMP	LINPTR,LINEND	;Move Right - end of buffer?
	BHI	22$			;yes - do nothing
	MOV	LINPTR,R1		;set up addr to move cursor to
	INC	R1			; = current pos + 1
	CALL	MOVEUP			;move cursor forward one char
	SOB	R4,LMOVER		;Do it as many times as repeat count says to.
22$:	JMP	GETCHR

LMOVEL:	CMP	LINPTR,LINBEG	;Move Left - Already at front?
	BLOS	38$			;yes - do nothing
	CMP	LINPTR,LINEND		;are we deleting at the end?  If so, ptr>end
	BLOS	35$			; no - just back up cursor
	CMPB	R0,#CTLH		;if cmd is ctrl-H, dont delete, just back up
	BEQ	35$
	TYPEIT	DELBS			; yes - delete char by typing BS+SPACE+BS
	DEC	LINPTR			;new buffer ptr.
	CLRB	@LINPTR			;put null char at new end of buffer
	DEC	LINEND			;new end of buffer
	BR	37$
35$:	MOV	LINPTR,R1		;set up new ptr addr = old - 1
	DEC	R1
	CALL	BACKUP			;back up cursor by 1 spot
37$:	SOB	R4,LMOVEL		;Repeat as specified by repeat count.
38$:	JMP	GETCHR
	
LTOEND:	MOV	LINPTR,R4	;To end of line - type chars to end of buffer.
	CALL	TYPBUF
	JMP	GETCHR

LTOFRO:	MOV	LINBEG,R1	;To front - Set addr to back up to = front of line
	CALL	BACKUP			;back up cursor to front of line
	JMP	GETCHR
	
LCLEAR:	CMP	LINEND,LINBEG	;Clear buffer - Any chars in the buffer?
	BLO	68$			; no - do nothing
	MOV	LINPTR,R4		;move cursor to end of line
	CALL	TYPBUF
	MOV	LINEND,R1		;calculate how many chars in the line
	SUB	LINBEG,R1		; = (data end) - (data start) + 1
	INC	R1
65$:	TYPEIT	DELBS			;delete the char at end (BS+SPACE+BS)
	SOB	R1,65$			;do it this many times
	CALL	INITED			;re-initialize variables
68$:	JMP	GETCHR

LSKIPR:	MOVB	R0,LASTCM	;Skip Right - Save so we can do a REPEAT command
	CALL	INCHR			;wait for next char to be typed, put in R0
	CMPB	R0,#ALT			;ignore cmd if ALT
	BNE	71$
	JMP	GETCHR
71$:	MOVB	R0,LASTSE		;save searched-for char for repeat cmd
LSKR1:	CMP	LINPTR,LINEND		;are we at end of the line?
	BHIS	78$			; yes - do nothing
	MOV	LINPTR,R1		;current ptr to R1
	INC	R1			;start at current+1
72$:	CMPB	(R1)+,R0		;is this the char to search for?
	BEQ	74$			; yes - go move cursor
	CMP	R1,LINEND		;any more chars to look at?
	BLOS	72$			; yes - keep looking
	BR	78$      		;not found - do nothing
74$:	DEC	R1			;we went 1 char too far (auto-incr R1)
	CALL	MOVEUP			;move cursor up to spot in R1.
	SOB	R4,LSKR1		;Repeat this as many times as desired.
78$:	JMP	GETCHR

LSKIPL:	MOVB	R0,LASTCM	;Skip Left - Save so we can do a REPEAT command
	CALL	INCHR			;wait for next char to be typed, put in R0
	CMPB	R0,#ALT			;ignore cmd if ALT
	BNE	81$
	JMP	GETCHR
81$:	MOVB	R0,LASTSE		;save searched-for char for repeat cmd
LSKL1:	CMP	LINPTR,LINBEG 	 	;are we at front of the line?
	BLOS	88$			; yes - do nothing
	MOV	LINPTR,R1		;current ptr to R1
82$:	CMPB	-(R1),R0		;is this the char to search for?
	BEQ	84$			; yes - go move cursor
	CMP	R1,LINBEG 		;any more chars to look at?
	BHI 	82$			; yes - keep looking
	BR 	88$     		;not found - ignore request.
84$:	CALL	BACKUP			;move cursor back to spot in R1.
	SOB	R4,LSKL1		;Repeat as specified.
88$:	JMP	GETCHR

LREPT:	MOVB	LASTSE,R0	;Repeat last SKIP - Set up last char searched for
	CMPB	LASTCM,#SKIPR		;Was last cmd SKIPR?
	BEQ	LSKR1			; yes - enter command sequence
	CMPB	LASTCM,#SKIPL		;SKIPL?
	BEQ	LSKL1			; yes - enter cmd seq
	JMP	GETCHR			;no last cmd - ignore request.

LWORD:	MOV	LINPTR,R1	;To next Word - Set up ptr into buffer
102$:	CMPB	(R1)+,#SPACE		;found space?
	BEQ	104$			; yes - now look for a non-space
	CMP	R1,LINEND		; no -  end of line?
	BLOS	102$			;   no - keep looking
	BR	108$  			;no space found - ignore request
104$:	CMPB	(R1)+,#SPACE		;now look for a non-space
	BNE	106$
	CMP	R1,LINEND
	BLOS	104$
	BR 	108$			; no non-space found - exit
106$:	DEC	R1			;back off R1 by 1 - we went too far.
     	CALL	MOVEUP			;Found non-space:  move cursor up to it.
	SOB	R4,LWORD		;Repeat as per specification.
108$:	JMP	GETCHR

LXPOSE:	MOV	LINPTR,R0	;Transpose previous two chars.
	SUB	LINBEG,R0		;Are we far enough into the line?
	CMP	R0,#2			;If diff is < 2, we're not - exit
	BLT	20$
	MOV	LINPTR,R1		;Put current pos'n in R1
	MOVB	-2(R1),R0		;Transpose chars in buffer first
	MOVB	-1(R1),-2(R1)
	MOVB	R0,-1(R1)
	MOVB	-2(R1),XPCHAR+2		;Move in xposed chars to type them out
	MOVB	-1(R1),XPCHAR+3
	TYPEIT	XPCHAR			;Type 2 BS's then 2 xposed chars
20$:	JMP	GETCHR
	
LBAD:	MOV	#BELL,R0	;Unrecognized - type a bell
	CALL	TYPCHR
	JMP	GETCHR

LDDT:	BPT			;For testing reasons - enter DDT
	JMP	GETCHR


DELBS:	.BYTE	BS,SPACE,BS,0	;Deleting backspace = BS + SPACE + BS
DELCHR:	.BYTE	SPACE,BS,0,0	;Delete current char & don't move cursor
XPCHAR:	.BYTE	BS,BS,0,0,0,0	;Move cursor back two spaces, then type 2 new chars
;	[INSTR:	LINSRT]

LINSRT:	CALL	INCHR		;Insert text - Wait for a char, put in r0
	CMPB	R0,#ALT			;end of insertion?
	BEQ	128$			; yes - we're all done
	CMPB	R0,#MINCH		;also end if it's not a character
	BLT	126$
	CMPB	R0,#MAXCH
	BGT	126$
	MOV	LINEND,R1		;move chars in buffer up a spot to make room
	INC	R1			;(move the null char too)
122$:	MOVB	(R1),1(R1)		;move a char up 
	CMP	R1,LINPTR		;are we done moving chars?
	BLOS	124$
	DEC	R1			;back off ptr to previous char.
	BR	122$
124$:	MOVB	R0,@LINPTR		;replace char with input char.
	INC	LINEND			;buffer extends one more char
	MOV	LINPTR,R1		;Back up cursor to previous place
	INC	R1			; Move it up one so next char follows last!
	MOV	LINPTR,R4		;now type out the new line
	CALL	TYPBUF
	CALL	BACKUP			;back up cursor
	BR	LINSRT			;wait for next char
126$:	JMP	MAINLP			;termination char encountered - process it.
128$:	JMP	GETCHR
	
;	[INSTR:	LDEL, LKILLR, LKILLL]

LDEL:	MOV	LINPTR,R1		;Now make R1 point to char to delete to.
	ADD	R4,R1			;Add # of chars to delete to pointer
	MOV	LINEND,R2		;Put end of text addr in R2 for compare
	INC	R2
	CMP	R1,R2     		;Are we past the end of the line?
	BLOS	LKILR1			 ;no - Enter KILLR sequence to do deletion.
      	JMP	GETCHR			;Nothing to delete - so do nothing...

LKILLR:	CALL	INCHR		;Kill Right to char - Read next char, put in R0
	CMPB	R0,#ALT			;ALT aborts the request
	BEQ	LKILRX
     	CMP	LINPTR,LINEND   	;Are we at end of the line?
	BHI 	LKILRX			; yes - do nothing
	CMPB	R0,#CR			;CR means kill to end of line
	BNE	141$			; if not, go look for char
	MOV	LINEND,R1		;Set addr to kill to.
	ADD	#2,R1			;Kills to R1-1. We want to kill to NULL char
	BR	144$
141$:	MOV	LINPTR,R1		;current ptr to R1
	INC	R1			;Start looking at one past the char
142$:	CMPB	(R1)+,R0		;is this the char to search for?
	BEQ	144$			; yes - go delete chars
	CMP	R1,LINEND		;any more chars to look at?
	BLOS	142$			; yes - keep looking
	BR 	LKILRX 			;not found - ignore request.
144$:	SOB	R4,142$			;Repeat as many times as desired.
       	DEC	R1			;Don't kill the char they typed.
LKILR1:	CMP	R1,LINPTR		;Any chars to delete?
	BLOS	LKILRX			; no - exit
	MOV	LINPTR,R3		;calculate how many chars deleted
	MOV	LINPTR,R2		;now delete chars from buffer. R2 = current
	SUB	R1,R3			; R3 = -(how many chars deleted)
	NEG	R3			; now R3 is correct (positive)
145$:	MOVB	(R1)+,(R2)+		;move a char down a few spots
	BNE	145$     		;Stop when we moved the null char at end.
	MOV	R2,LINEND		;save new end of data 
	SUB	#2,LINEND		; we went 2 chars too far.
	MOV	LINPTR,R4		;Set addr of string to type = rest of line.
	CALL	TYPBUF			;Type new string.  Note: R4 isn't changed!
	ADD	R3,LINPTR		;account for spaces we're about to type
	MOV	#SPACE,R0		;now type a few spaces to clear chars
147$:	CALL	TYPCHR			; at the end of the line
	SOB	R3,147$
	MOV	R4,R1			;Set up R1 to where we want cursor to go
	CALL	BACKUP			;back up cursor to final place
LKILRX:	JMP	GETCHR

LKILLL:	CALL	INCHR		;Kill Left to char - Read next char, put in R0
	CMPB	R0,#ALT			;ALT aborts the request
	BEQ	138$
     	CMP	LINPTR,LINBEG   	;are we at front of the line?
	BLOS	138$			; yes - do nothing
	CMPB	R0,#CR			;CR means kill to beginning of line
	BNE	131$			; if not, go look for char
	MOV	LINBEG,R1		;Set addr to kill to.
	DEC	R1			;kills to R1+1.
	BR	134$
131$:	MOV	LINPTR,R1		;current ptr to R1
132$:	CMPB	-(R1),R0		;is this the char to search for?
	BEQ	134$			; yes - go delete chars
	CMP	R1,LINBEG		;any more chars to look at?
	BHI 	132$			; yes - keep looking
	BR 	138$  			;not found - ignore request.
134$:	SOB	R4,132$			;Repeat as specified by Repeat Count.
     	INC	R1			;Don't kill the char they typed.
	CMP	R1,LINPTR		;Any chars to delete?
	BHIS	138$			; no - exit
	MOV	LINPTR,R3		;calculate how many chars deleted
	MOV	LINPTR,R2		;now delete chars from buffer. R2 = current
	SUB	R1,R3			; R3 = how many chars deleted
       	CALL	BACKUP			;back up cursor to char.
135$:	MOVB	(R2)+,(R1)+		;move a char down a few spots
	BNE	135$     		;Stop when we moved the null char at end.
	MOV	R1,LINEND		;save new end of data 
	SUB	#2,LINEND		; we went 2 chars too far.
	MOV	LINPTR,R4		;Set addr of string to type = rest of line.
	CALL	TYPBUF			;Type new string.  Note: R4 isn't changed!
	ADD	R3,LINPTR		;account for spaces we're about to type
	MOV	#SPACE,R0		;now type a few spaces to clear chars
137$:	CALL	TYPCHR			; at the end of the line
	SOB	R3,137$
	MOV	R4,R1			;Set up R1 to where we want cursor to go
	CALL	BACKUP			;back up cursor to final place
138$:	JMP	GETCHR
	
;	[INSTR:	LGETM, LDEFM]

LGETM:	CALL	INCHR		;Get macro definition - see which one
	CMPB	R0,#ALT			;Abort?
	BEQ	20$
	CMPB	R0,#'0			;Is it valid?
	BLT	10$			 ;must be between 0 and 9
	CMPB	R0,#'9
	BGT	10$
	SUB	#'0,R0			;Make it between 0 and 11, octal.
	ASL	R0			;Multiply by two to make it even.
	MOV	LMACAD(R0),R1		;Get addr of beginning of macro
	TST	R1			;Is it defined yet?
	BEQ	10$			 ;no - type bell to inform user
	MOV	R1,LMACPT		;Set up macro pointer for INCHR to use
	INC	LMODE			;mode 1 means we're expanding a macro
	BR	20$
10$:	MOV	#BELL,R0		;Type a bell to complain
	CALL	TYPCHR
20$:	JMP	GETCHR

LDEFM:	TYPEIT	GET1		;Define a macro - ask which one
10$:	CALL	INCHR			;Read response - ALT to abort else 0-9
	CMPB	R0,#ALT
	BEQ	100$			;ALT = abort, do nothing
	CMPB	R0,#'0			;Validate the macro number.
	BLT	15$			 ;must be between 0 and 9
	CMPB	R0,#'9
	BLE	17$
15$:	MOV	#BELL,R0		;Ring bell - invalid macro name
	CALL	TYPCHR
	BR	10$			;Go retry
17$:	CALL	TYPCHR			;Echo what macro it is.
     	SUB	#'0,R0			;Make it between 0 and 11, octal.
	ASL	R0			;Make macro # even by multiplying by 2
	MOV	R0,LMSAVE		;Save the macro addr offset for later.
	MOV	LMACAD(R0),R1		;Retreive current macro ptr
	MOV	LMEND,LMACAD(R0)	;and set up new macro addr
	TST	R1			;Is it currently defined?
	BEQ	30$			 ;no - don't need to erase it.	
;Now clear out previous macro def.
	MOV	R1,R2			;Put macro addr in R2 & look for end.
20$:	TSTB	(R2)+			;End of macro?
	BNE	20$			 ;no - keep looking
	MOV	R2,R4
	SUB	R1,R4			;R4 now contains macro length
	MOV	#LMACAD,R0		;Now fix up the macro table:  If any addr
	MOV	#10.,R3			 ;is higher than the macro we just
22$:	CMP	(R0),R1			 ;deleted, subtract the length of the
	BLOS	23$			 ;deleted macro from it.
	SUB	R4,(R0)
23$:	TST	(R0)+
	SOB	R3,22$
	SUB	R4,LMEND		;Update new end of table.
25$:	MOVB	(R2)+,(R1)+		;Now move all the other macro defs down
	BNE	25$
	TSTB	(R2)			;Is this the end of the macro table?
	BNE	25$			 ;if so, there are 2 nulls in a row.
;Now ask for macro definition.
30$:	TYPEIT	GET2			;Now ask for macro def'n
	MOV	LMEND,R2		;Put starting macro addr in R2
32$:	CALL	INCHR			;Read a char
	CMPB	R0,#ALT			;end of macro def'n
	BEQ	80$			 ;yes - quit
	MOV	#-1,LMSAVE		;This means macro is not null (just ALT)
	CMPB	R0,#ALT			;Now see if char is a control char.
	BLT	35$			;Is it a control char?  Don't echo if so.
	CMPB	R0,#RUBOUT		;RUBOUT char?  This is special
	BEQ	45$
	CALL	TYPCHR			;else echo the char.
	BR	70$
35$:	MOV	R0,R1			;We'll look in dispatch tbl to see if valid
	ASL	R1
	CMP	DISPTB(R1),#LBAD	;If its dispatch addr is LBAD, it's no good
	BEQ	37$			;If char is not in table, ring bell
    	CMPB	R0,#CR			;Some control chars are invalid in macros
	BEQ	37$			 ;like CR
	CMPB	R0,#CTLG		 ;and CTL-G (define macro)
	BEQ	37$
	CMPB	R0,#CTLZ		 ;and CTL-Z (define macro)
	BNE	40$
37$:	MOV	#BELL,R0		 ;So ring bell to inform
	CALL	TYPCHR
	BR	32$
40$:	MOV	R0,R1			;Now we'll echo "↑C" for control char C
     	ADD	#'@,R1			;Make into a normal char
	MOVB	R1,MACECH+1		;Move into place to type from
	TYPEIT	MACECH
	BR	70$
45$:	TYPEIT	MACBS			;They typed RUBOUT - echo <BS>
70$:	MOVB	R0,@LMEND		;Store this char
	INC	LMEND			;and update next loc'n address
	BR	32$			;go get another macro char.
80$:	CMP	LMSAVE,#-1		;Was this a null macro? (just ALT)?
	BEQ	82$			 ;If save=-1, it's not - continue normally
	MOV	LMSAVE,R0		;Null macro!!  Clear entry in LMACAD table
	CLR	LMACAD(R0)
	BR	100$			;Don't make the buffer any longer.
82$: 	CLRB	@LMEND			;Set null byte at end of macro
	INC	LMEND			;and make it point to next available spot
100$:	CALL	CRLF			;Type a CR+LF
	JMP	LRETYP			;retype the buffer & get commands again


GET1:	.BYTE	15,12
	.ASCIZ	/Define macro.  Name (0-9, ALT=abort): /
GET2:	.BYTE	15,12
	.ASCIZ	/Define it (end with ALT): /
MACECH:	.BYTE	136,0,0,0
MACBS:	.ASCIZ	/<BS>/
.EVEN
; DATA DEFINITIONS

LINBUF:	.BLKB	BUFLEN		;LINE BUFFER.
LINBEG:	.WORD	LINBUF		;ALWAYS POINTS TO BEGINNING OF BUFFER.
LINPTR:	.WORD	0		;PTR INTO PLACE TO PUT NEXT CHAR.
LINEND:	.WORD	0		;POINTS TO LAST CHAR IN BUFFER.
LINRPT:	.WORD	0		;HOW MANY TIMES TO REPEAT THE COMMAND  RRR

LASTCM:	.BYTE	0		;LAST COMMAND INPUT
LASTSE:	.BYTE	0		;LAST CHAR WE SEARCHED FOR

LMODE:	.WORD	0		;0=normal mode(tty), 1=read from macro
LMACPT:	.WORD	0		;Points to current place in the macro we're reading
LMEND:	.WORD	LMACBU		;Points to next open spot in macro buffer.
LMSAVE:	.WORD	0		;If macro def isn't null, this is -1.
LMACAD:	.WORD	0,0,0,0,0,0,0,0,0,0	;Points to macro beginning addr (in LMACBU)
LMACBU:	.BLKB	100.		;Space to hold macros.

PATCH:	.BLKW	100.		;PATCH AREA

	.END	START